NewGridFloatFromFile Subroutine

private subroutine NewGridFloatFromFile(layer, fileName, fileFormat, variable, stdName, time)

read a grid from a file. List of supported format: ESRI_ASCII: ESRI ASCII GRID ESRI_BINARY: ESRI BINARY GRID NET_CDF: NetCDF CF compliant

Arguments

Type IntentOptional Attributes Name
type(grid_real), intent(out) :: layer

gridreal to return

character(len=*), intent(in) :: fileName

file to read

integer(kind=short), intent(in) :: fileFormat

format of the file to read

character(len=*), intent(in), optional :: variable

variable to read

character(len=*), intent(in), optional :: stdName

standard name of the variable to read

type(DateTime), intent(in), optional :: time

time of the grid to read


Source Code

SUBROUTINE NewGridFloatFromFile &
!
(layer, fileName, fileFormat, variable, stdName, time)

IMPLICIT NONE

!Arguments with intent(in):
CHARACTER (LEN = *), INTENT(IN) :: fileName  !! file to read
INTEGER (KIND = short), INTENT(IN) :: fileFormat  !! format of the file to read
CHARACTER (LEN = *), OPTIONAL, INTENT(in) :: variable  !!variable  to read
CHARACTER (LEN = *), OPTIONAL, INTENT(in) :: stdName  !!standard name of 
                                                      !!the variable  to read
TYPE (DateTime), OPTIONAL, INTENT(in) :: time  !!time of the grid to read

!Arguments with intent(out):
TYPE (grid_real), INTENT(OUT)     :: layer  !!gridreal to return

!Local variables:

!------------end of declaration------------------------------------------------

IF ( fileformat == ESRI_ASCII ) THEN
  CALL NewGridFloatFromESRI_ASCII (fileName, layer)
ELSE IF ( fileformat == ESRI_BINARY ) THEN
  CALL NewGridFloatFromESRI_BINARY (fileName, layer)
ELSE IF ( fileformat == NET_CDF ) THEN
  IF (PRESENT(stdName)) THEN
    IF (PRESENT (time)) THEN
      CALL NewGridFloatFromNetCDF (layer, fileName, stdName = stdName, time = time)
    ELSE
      CALL NewGridFloatFromNetCDF (layer, fileName, stdName= stdName)
    END IF
  ELSE IF (PRESENT(variable)) THEN
    IF (PRESENT (time)) THEN
      CALL NewGridFloatFromNetCDF (layer, fileName, variable = variable, time = time)
    ELSE
      CALL NewGridFloatFromNetCDF (layer, fileName, variable = variable)
    END IF
  END IF
ELSE
  CALL Catch ('error', 'GridLib',  &
               'unknown option in reading file grid: ',  &
               code = unknownOption, argument = fileName )
END IF

END SUBROUTINE NewGridFloatFromFile